home *** CD-ROM | disk | FTP | other *** search
-
-
- PAGE 60,132
- TITLE EPSON MX-GRAFTRAX PrtSc, V 2.3a
- ; GRAF.COM 3/12/83
- ; INTERRUPT REPLACEMENT FOR PRINT SCREEN FUNCTION ON IBMPC(tm)
- ; =====> N O T I C E <=======
- ; THIS PROGRAM IS SUPPLIED FOR YOUR PERSONAL AND NON-COMMERCIAL
- ; USE ONLY. NO COMMERCIAL USE PERMITTED. USERS OF THIS PROGRAM
- ; ARE GRANTED LIMITED RIGHTS TO REPRODUCE AND DISTRIBUTE THIS
- ; PROGRAM. IT MAY NOT BE SOLD. PROVIDING THIS PROGRAM FOR
- ; CONSIDERATION ANY SORT, INCLUDING COPYING OR DISTRIBUTION FEES,
- ; IS SPECIFICALLY PROHIBITED. THE AUTHOR CANNOT ASSUME RESPONSIBILITY
- ; FOR DAMAGES, REAL OR IMAGINED, RESULTING FROM THE USE OF THIS PROGRAM.
- ; =====> ENDNOTICE <=========
- ;
- ; PLEASE SEND PROBLEM REPORTS AND SUGGESTIONS TO:
- ; MARTY SMITH
- ; 310 CINNAMON OAK LANE
- ; HOUSTON, TEXAS 77079
- ; SOURCE ST2259, COMPUSERVE 72155,1214
- ; (713) 661-1241 Office, (713) 464-6737, Home.
- ;
- ; THIS PROGRAM ORIGINALLY DESIGNED FOR EPSON-MX(tm) SERIES PRINTERS
- ; WITH GRAFTRAX80(tm) AND GRAFTRAX+(tm) BIT-PLOT GRAPHIC CAPABILITES.
- ; ======> Now modified with conditional compilation and macros for
- ; ======> c.itoh(tm) model 8510a and other printers with bit-plot
- ; ======> capabilities. See the macro definitions and equates following
- ; ======> these messages.
- ;
- ; CHANGE HISTORY:
- ; 9/18/82 - Buffer in routine for a line of bit-plot bytes to allow for
- ; checking for blank lines replaced by pre-scan routine, saving space.
- ; 1/24/83 - Modifications for conditional assembly with other printers
- ; and C.ITOH 8510a.
- ; 1/24/83 - Improved error checking for out-of-paper and I/O errors
- ; involving printer.
- ; 1/24/83 - Bug in error check corrected, occuring when routine does
- ; error exit and is then called again, resulting in bit-plot data sent in
- ; regular mode.
- ; 3/12/83 - Allow calling as a subroutine. i.e. no shift key depressed.
- ; Defaults to small print mode. Can be poked for LARGE.
- ;
- ; THE IBM MACRO ASSEMBLER(tm) AND LINK(tm) WILL PRODUCE
- ; GRAF.EXE, WHICH MUST BE CONVERTED TO A .COM PROGRAM BY
- ; THE COMMAND FROM DOS -EXE2BIN-.
- ; do this:
- ; X>EXE2BIN GRAF.EXE GRAF.COM
- ;
- ; Features:
- ; Accepts ESC key exit, prescans to test for blank line
- ; left shift prtsc = small graphics, right shift prtsc = big
- ; Runs as a .COM type program under dos
- ; resident until power down or reset.
- ; 1 = screen sent horiz. 320 bits in 480 mode
- ; 2 = screen sent vert. 400 bits double printed in 480 mode
- ; ************** 1 mode **********************
- ; DL = masking character
- ; DH = count of 25 (physical lines)
- ; CX = counter for each line (80)
- ; DS = used to index screen at 'b8000'
- ; These regs must be preserved during routine
- ; (increment each line by adding '14' hex to ds for para
- ; boundary of 320 bytes '140')
- ; ************** 2 mode *********************
- ; DH = count of 40 (physical lines)
- ; CX = counter for each line (100)
- ; SI = index to screen via ds
- ; These regs must be preserved during routine
- ; all output to printer is done from routine -send2-, which uses
- ; bios routine int 17h, and provides safe error exit.
- ;
- ; GRAF.COM is designed with the idea that the user's main program is the
- ; primary function and GRAF.COM should not cause problems of its own.
- ; The author has tried his best to send control back to the main program in
- ; the case of errors involving the printer, and to make the program as easy
- ; to use as possible.
- ;
- ; =======================================================
- ; = USER MODIFICATION SECTION. =
- ; = If your printer can treat a byte of data to =
- ; = control the wires on the dot-matrix head you =
- ; = can probably get this working with your printer =
- ; = If you have Epson Graftrax or a C.Itoh 8510a, =
- ; = just set the two equates indicated to -true- =
- ; = and compile. Otherwise get out your manual =
- ; = and put the code indicated in the -other- =
- ; = section and set -other- to -true-. =
- ; = **> The title message starts at label =
- ; = **> -buffer-. If you set for another =
- ; = **> printer you should change the =
- ; = **> greeting to indicate which printer =
- ; = ===> ONLY SET *ONE* CONDITION TO -TRUE- or you =
- ; = will have a real mess! marty smith =
- ; =======================================================
-
- TRUE EQU 1 ; DON'T CHANGE THESE!
- FALSE EQU 0
-
- ; ===============> A L L U S E R S <===================
- ; ====> SET ONE AND ONLY ONE OF THE FOLLOWING THREE <=====
-
- EPSON EQU TRUE
- CITOH EQU FALSE
- OTHER EQU FALSE
-
- ; Each bit of a byte is mapped to the wire head of the printer.
- ; If the Epson MX is sent 80h (bit 7), the TOP wire makes a dot.
- ; If the C.ITOH is sent 01h (bit 0), the TOP wire makes a dot.
- ; ===============> A L L U S E R S <===================
- ; =====> SET ONE AND ONLY ONE OF THE FOLLOWING TWO <======
-
- BIT7 EQU TRUE
- BIT0 EQU FALSE
- ; BIT7 is TRUE for EPSON
- ; BIT0 is TRUE for CITOH
-
- ; *****************************
- ; * START of -OTHER- SECTION *
- ; *****************************
- ;
- ; ALL routines must set either BIT7 or BIT0.
- ; above. If your printer can't see bit 7 or 0 as the top wire, you
- ; will probably have quite a time getting this routine to work.
- ;
- ; OLINE Resets line spacing so that the print head
- ; will make a continuous line DOWN the page.
- ; This is the sequence to set the EPSON for this. (ESC A 8)
- ; SEND2 sends the byte in AL to the printer for ALL routines.
- ; It uses the INT 17h routine in order to avoid DOS's extra line
- ; feeds and CR's. Set for LPT1: Change SEND2 to redirect. DX=0=LPT1,1=LPT2
- OLINE MACRO
- MOV AL,27
- CALL SEND2
- MOV AL,65
- CALL SEND2
- MOV AL,8
- CALL SEND2
- ENDM
-
- ; ORLINE restores the printer to normal line spacing
- ; Example is for EPSON (ESC 2)
- ORLINE MACRO
- MOV AL,27
- CALL SEND2
- MOV AL,'2'
- CALL SEND2
- ENDM
-
- ; ORESET reinitializes the printer to default settings, spacings,
- ; current line becomes Top of Form.
- ; Is used by LARGE print to allow a series to be printed
- ; on separate pages. It can be modified by getting rid of label
- ; TOF: up to but not including JMP DONE, which is the exit from
- ; the whole routine. Example is for EPSON. (ESC @)
- ORESET MACRO
- MOV AL,27
- CALL SEND2
- MOV AL,'@'
- CALL SEND2
- ENDM
-
- ; BP1 initiates bit-plot graphics. It tells the printer
- ; that the next xxx bytes are to be considered bit-plots and not
- ; regular characters. The small print routine sends 320 bit plot bytes
- ; to the printer. On the EPSON this is:
- ; ESC K 64 1 hex 1b 4b 40 1 > 1*256+64=320
- ; --> the first part indents the page with ordinary spaces
- ; --> to find spaces take TOTAL_DOTS_PER_LINE - 320. Then / BITS_PER_CHARACTER
- ; --> Divide this by two and you have the spaces to indent
- BP1 MACRO
- MOV CX,13 ; EPSON ( we've got 320 dots and 480 to work with
- INLOP: MOV AL,20H ; 480-320=160 / 6 dots per char. = 26.67 extra
- CALL SEND2 ; so indent the picture 13 spaces to center
- LOOP INLOP
- MOV AL,27
- CALL SEND2
- MOV AL,75
- CALL SEND2
- MOV AL,64
- CALL SEND2
- MOV AL,1
- CALL SEND2
- ENDM
-
- ; BP2.
- ; The LARGE print sends 400 bit plot bytes to the printer. On the EPSON:
- ; ESC K 144 1 hex 1b 4b 90 1 > 1*256+144=400
- ; FIND YOUR INDENT FOR 400 BITS
- BP2 MACRO
- MOV CX,6 ; EPSON ( we've got 400 dots and 480 to work with
- INLOP2: MOV AL,20H ; 480-400=80 / 6 dots per char. = 13.33 extra
- CALL SEND2 ; so indent the picture 6 spaces to center
- LOOP INLOP2
- MOV AL,27
- CALL SEND2
- MOV AL,75
- CALL SEND2
- MOV AL,144
- CALL SEND2
- MOV AL,1
- CALL SEND2
- ENDM
-
- ; ****************************
- ; * END OF -OTHER- SECTION *
- ; ****************************
-
- ; ***************> START OF ACTUAL CODE <*****************
-
- CSEG SEGMENT 'CODE'
- ASSUME CS:CSEG
- ORG 100H ; set up for .COM conversion
- INIT PROC FAR ; we're an interrupt routine
- JMP INITIAL ; so we have to set up first
- BUFFER DB ' GRAFTRAX.COM v1.2',10,13
- DB 'EPSON MX-80 GRAFTRAX(tm) Screen Printer.',13,10
- DB ' Left Sh. PrtSc. = LARGE GRAPHICS',13,10
- DB ' Right Sh. PrtSc. = small graphics',13,10
- DB ' Text screen uses regular ROM routine.',13,10
- DB ' ESCape will exit GRAPHICS print.',13,10,'$'
- GOWAIT DW 0
- WHERESI DW 0
- PTFLAG DB 0
- ONEOR2 DB 0
- DSTOR DW 0
- FUDGE DD 0
- INITIAL:
- MOV AX,0 ; GET ADDR OF
- MOV DS,AX ; PRINT SCREEN ROUTINE
- MOV SI,14H ; IN ROM
- MOV AX,[SI] ; from interrupt table in ram
- MOV DX,AX ; in case they change the ROM's!
- INC SI
- INC SI
- MOV AX,[SI]
- MOV DS,AX
- MOV AL,0F1H ; MOVE IT TO
- MOV AH,25H
- INT 21H ; INT F1H described in Tech. Manual as unused vector
- MOV AX,CS ; RESET INT 5
- MOV DS,AX ; TO POINT TO
- MOV AX,OFFSET START ; THIS ROUTINE
- MOV DX,AX
- MOV AL,5
- MOV AH,25H ; DOS routine to reset int. vector
- INT 21H
- MOV AX,CS
- MOV DS,AX
- MOV AX,OFFSET BUFFER
- MOV DX,AX
- MOV AH,9
- INT 21H ; PRINT GREETING
- MOV AX,OFFSET LAST ; last address here
- MOV DX,AX
- INC DX
- INT 27H ; TERMINATE BUT STAY RESIDENT
- INIT ENDP
- ; ---> ACTUAL INTERRUPT ROUTINE STARTS HERE <---
- START PROC FAR ; Start of main routine--Shift Prt.Sc hit.
- ASSUME CS:CSEG
- STI ; This follows ROM routine real close
- PUSH DS
- PUSH AX ;SAVE REGS
- PUSH BX
- PUSH CX
- PUSH DX
- PUSH DI
- PUSH SI
- PUSH BP
- MOV BP,SP ; Save in case of error for reset
- MOV AX,50H ; Check here first to see if
- MOV DS,AX ; routine is already in progress
- MOV SI,0 ; otherwise it will be a mess.
- MOV AL,01H
- CMP [SI],AL
- JNZ NXTS ; if not we're go for routine
- JMP EXIT ; otherwise go back home.
- NXTS: MOV [SI],AL ; if we're go don't let us start again until done.
- MOV AH,15 ; Get the current video state.
- INT 10H ; from the ROM routine,
- CMP AL,4 ; AL=4-6 are all graphics so we're OK
- JZ GRAPHIC
- CMP AL,5
- JZ GRAPHIC
- CMP AL,6
- JZ GRAPHIC
- MOV AL,0 ; else reset and go to ROM routine.
- MOV [SI],AL
- INT 0F1H ; this is where we stored the ROM routine entry.
- JMP EXIT ; Do the ROM routine but come back here to leave.
- GRAPHIC:
- MOV AX,40H ; Get the keyboard shift flag
- MOV DS,AX ; segment
- MOV SI,17H ; and address
- MOV AX,[SI] ; pick it up
- AND AX,3 ; get rid of other stuff
- CMP AX,0 ; Mod. to create default small
- JNZ GR1 ; for case where routine is called as
- MOV AX,1 ; a subroutine.
- GR1: MOV CS:ONEOR2,AL ; store for later
- PUSH AX ; also here
- MOV AL,0 ; make sure this starts out as NO print.
- MOV CS:PTFLAG,AL
- MOV DL,00H ; These bits indicate whether R or L Shift is down
- MOV DH,19H ; 25 lines of graphic dots at 8 dots per line
- MOV AX,0B800H ; stored in DX
- MOV DS,AX ;SET UP FOR SCREEN PEEK
- ; Printer setup section to change line spacing to 8/72" for continuous dots
- IF EPSON
- MOV AL,27 ; ESC
- CALL SEND2 ; goes out through INT 17h to avoid DOS processing
- MOV AL,65 ; A
- CALL SEND2
- MOV AL,8 ; 8
- CALL SEND2
- ENDIF
- IF CITOH ; ESC T 16
- MOV AL,27 ; ESC
- CALL SEND2 ; goes out through INT 17h to avoid DOS processing
- MOV AL,'T' ; T
- CALL SEND2
- MOV AL,'1' ; 1
- CALL SEND2
- MOV AL,'6' ; 6
- CALL SEND2
- MOV AL,27
- CALL SEND2
- MOV AL,62 ; Set printer to unidirectional for dot alignment
- CALL SEND2
- ENDIF
- IF OTHER
- OLINE
- ENDIF
- POP AX ; get back which routine
- CMP AL,2 ; Left Shift Prt Sc means LARGE graphic print
- JZ MAIN2 ; so hop over there if so.
- ; START OF small GRAPHICS PRINT ROUTINE.
- ; This routine scans across the screen from left to right,
- ; building an EPSON bit plot byte out of IBM screen dots.
- ; EPSON wire head IBM screen color dots
- ; TOP o 128 80h bit 7 | 00 | 01 | 10 | 11 | = 4 dots, one byte
- ; o 64 40h " 6
- ; one o 32 20h " 5 ibm dots go one raster line then the next
- ; bit o 16 10h " 4 EVEN line, ie 0, 2, 4 etc.
- ; plot o 8 08h " 3
- ; byte o 4 04h " 2 then you go back and do 1, 3, 5 etc.
- ; o 2 02h " 1
- ; BOTTOM o 1 01h " 0 At loc. 0000h are 4 dots, 0,0|0,1|0,2|0,3
- ; At loc. 2000h are 4 dots, 1,0|1,1|1,2|1,3
- ;
- MAIN: MOV CX,80 ; 80 x 4 = 320 dots.
- MLOOP: MOV DL,0C0H ; 11000000b
- CALL TST4 ; see if this comes back <> 0
- MOV AL,AH ; we are testing bit patterns for one screen byte
- CALL SEND ; don't send to printer unless something to send
- MOV DL,30H ; 00110000b
- CALL TST4 ; each byte is 4 dots
- MOV AL,AH ; so we test for each dot in a byte
- CALL SEND ; send sets PTFLAG if there is a dot on the line
- MOV DL,0CH ; 00001100b
- CALL TST4 ; then resets to start of line and starts printing
- MOV AL,AH ; AL is the bit plot byte being built
- CALL SEND
- MOV DL,03H ; 00000011b
- CALL TST4 ; TST4 scans down 8 screen dot lines each time called
- MOV AL,AH
- CALL SEND
- LOOP MLOOP ; 80 bytes make 320 dots
- CALL LFCR ; this is a good old regular line feed/carriage return
- CALL BREAK? ; see if someone hit ESC key. If so take early exit
- OR AL,AL
- DEC DH ; DL is line counter
- CMP DH,0 ; when it goes 0 we're through
- JZ DONE ; reset everything and do an IRET
- MOV AX,DS ; otherwise bump the SEGMENT reg so that location
- ADD AX,14H ; 0 is the start of the next line
- MOV DS,AX ; X'140' = 320
- JMP MAIN ; and do this 80 times (80x4=320)
- DONE: MOV AX,0
- ; This is the common exit for both routines, Printer is restored.
- DONE1: PUSH AX ; save AX cause it has error exit flag
- ; EPSON command to reset printer to 6 lines/in. = ESC 2 (1b 32)
- IF EPSON
- MOV AL,27 ; RESET PRINTER, RESTORE REGS
- CALL SEND2
- MOV AL,32H
- CALL SEND2
- ENDIF
- ; FOR CITOH MAKE SURE BIDIRECTIONAL PRINTING IS RESTORED
- IF CITOH
- MOV AL,27
- CALL SEND2
- MOV AL,'A'
- CALL SEND2
- MOV AL,27
- CALL SEND2
- MOV AL,60
- CALL SEND2
- ENDIF
- IF OTHER
- ORLINE
- ENDIF
- EDONE: MOV AX,50H ; Set end of PrtSc indication
- MOV DS,AX ; OK to come back and do again
- MOV SI,0
- POP AX
- MOV [SI],AL
- EXIT: POP BP
- POP SI ; restore regs and return to caller
- POP DI
- POP DX
- POP CX
- POP BX
- POP AX
- POP DS
- IRET ; were an interrupt routine so we IRET
- ; START OF LARGE PRINT ROUTINE
- ; +-------------+
- ; | ^ ^ | This time we scan from 199,0 to 0,0
- ; | ^ ^ | and go across
- ; | ^ ^ | o o x x o x x x These are representations
- ; | | | | o o o o x o x x of one color dot.
- ; +-------------+ 0 1 2 3 Palettes
- MAIN2: MOV DH,80 ; we have 80 colunms x 25 lines here
- MOV CS:WHERESI,3EF0H ; SI is our index
- MOV SI,CS:WHERESI
- MAIN2A: MOV CX,64H ; 100
- MLOOP2: MOV AL,[SI] ; idea is to get a byte starting at screen BOTTOM
- IF BIT0
- CALL REVERSE ; Bits have to be reversed on wire 0 type
- ENDIF
- CALL SEND ; send it since these resemble bit plot bytes
- CALL FLIPFLOP ; then reverse(sort of) this byte and send it
- CALL SEND ; again.
- MOV CS:GOWAIT,SI ; store SI for next EVEN raster line
- SUB SI,2000H ; subtract 2000h for the next ODD raster line
- MOV AL,[SI] ; and do the same here
- IF BIT0
- CALL REVERSE
- ENDIF
- CALL SEND
- CALL FLIPFLOP
- CALL SEND
- MOV SI,CS:GOWAIT ; get back the EVEN line
- SUB SI,80 ; advance UP the screen one line (say 199,0 to 197,0)
- LOOP MLOOP2 ; and do this 100 times
- CALL LFCR ; finished with one line we send normal line-end
- CALL BREAK? ; check for an ESC if we want to abort
- OR AL,AL ; clear flags
- DEC DH ; DH is our line counter,
- CMP DH,0 ; when it goes 0 we're done.
- JZ TOF ; so we'll try to reset Top of Form and exit
- INC CS:WHERESI ; else go to the next byte location
- MOV SI,CS:WHERESI ; store
- JMP MAIN2A ; and do again
- TOF: MOV CX,19 ; tof restores page to 11 inches from where it started
- TOFL: MOV AL,13 ; send a bunch of cr's and lf's
- CALL SEND2 ; put BREAK? in here somehow
- MOV AL,10
- CALL SEND2
- CALL BREAK? ; check for early exit
- LOOP TOFL ; on and on.
- ; This restores the EPSON to 6 lines per inch
- ; ESC @ = Restore all settings to default
- IF EPSON
- MOV AL,27 ; esc
- CALL SEND2
- MOV AL,64 ; @
- CALL SEND2
- ENDIF
- ; IF CITOH ; No equivalent to Epson ESC @
- ; MOV AL,27 ; for CITOH
- ; CALL SEND2 ; so just reset line feed pitch
- ; MOV AL,'A' ; this is done by DONE anyway
- ; CALL SEND2 ; so leave open if someone wants to patch
- ; ENDIF
- IF OTHER
- ORESET
- ENDIF
- JMP DONE ; clean up and back to caller.
- START ENDP
- SEND2 PROC NEAR ; BIOS routine to print the character in AL
- PUSH AX
- MOV AH,00H ; 0=print, 1=initialize port, 2=read status to AH
- PUSH DX
- MOV DX,0 ; DX specifies printer 0 (LPT1:)
- INT 17H ; BIOS used instead of DOS because DOS sends
- POP DX ; CR/LF's in the middle of the bit-plots
- TEST AH,29h ; check for timeout or errors or out-of-paper
- POP AX
- JNZ ERRET
- RET
- ERRET: MOV AX,00FFH ; Flag for printer foulup
- MOV SP,BP
- PUSH AX
- JMP EDONE ; special abort
- SEND2 ENDP
- ; EPSON bit plots operate at 480 or 960 dots across the page
- ; called by ESC K 'low byte';'high byte'
- ; i.e. 300 dots would be 256+44 or 012CH
- ; This is sent to the EPSON as --> 1b 4b 2c 01
- ; or in decimal --> 27 75 44 1
- INDENT PROC NEAR
- PUSH CX ; 13 SPACES IN TO CENTER
- IF EPSON
- MOV CX,13 ; PICTURE ( we've got 320 dots and 480 to work with
- INLOP: MOV AL,20H ; 480-320=160 / 6 dots per char. = 26.67 extra
- CALL SEND2 ; so indent the picture 13 spaces to center
- LOOP INLOP
- ; ESC K 64 1 = 256+64=320 bit plot type bytes on the way
- MOV AL,27 ; SEQUENCE TO SET UP 320
- CALL SEND2 ; BIT PLOTS IN 480 MODE
- MOV AL,75 ; OF MX-80
- CALL SEND2 ; This is the set-up for the small print
- MOV AL,64
- CALL SEND2
- MOV AL,1
- CALL SEND2
- ENDIF
- IF CITOH
- MOV AL,27 ; ESC N = Pica pitch
- CALL SEND2
- MOV AL,'N'
- CALL SEND2
- MOV CX,20 ; PICTURE ( we've got 320 dots and 640 to work with
- INLOP: MOV AL,20H ; 640-320=320 / 8 dots per char. = 40 extra
- CALL SEND2 ; so indent the picture 13 spaces to center
- LOOP INLOP
- ; ESC S 0320 = 320 bit plot type bytes on the way
- MOV AL,27 ; SEQUENCE TO SET UP 320
- CALL SEND2 ; BIT PLOTS IN 640 MODE
- MOV AL,'S' ; OF CITOH
- CALL SEND2 ; This is the set-up for the small print
- MOV AL,'0' ; Would love to try to use all 640 bits here
- CALL SEND2 ; but have no way of testing routine.
- MOV AL,'3'
- CALL SEND2
- MOV AL,'2'
- CALL SEND2
- MOV AL,'0'
- CALL SEND2
- ENDIF
- IF OTHER
- BP1
- ENDIF
- POP CX
- RET
- INDENT ENDP
- ; This is indent for LARGE print
- ; This time we have 400 bit plots to send (200 lines x 2)
- ; 480-400=80 / 6 = 13.3 extra
- INDENT2 PROC NEAR
- PUSH CX
- IF EPSON
- MOV CX,6 ; so indent 6 character type spaces
- INLOP2: MOV AL,20H
- CALL SEND2
- LOOP INLOP2
- ; ESC 27 K 144 1 = 256+144=400 bit-plots
- MOV AL,27
- CALL SEND2
- MOV AL,75
- CALL SEND2
- MOV AL,144
- CALL SEND2
- MOV AL,1
- CALL SEND2
- ENDIF
- ; 640-400=240 / 8 = 30 EXTRA characters
- IF CITOH
- MOV AL,27 ; ESC N = Pica pitch
- CALL SEND2
- MOV AL,'N'
- CALL SEND2
- MOV CX,15 ; PICTURE ( we've got 400 dots and 640 to work with
- INLOP2: MOV AL,20H ; 640-400 / 8 dots per char. = 30 extra
- CALL SEND2 ; so indent the picture 15 spaces to center
- LOOP INLOP2
- ; ESC S 0400 = 400 bit plot type bytes on the way
- MOV AL,27 ; SEQUENCE TO SET UP 400
- CALL SEND2 ; BIT PLOTS IN 640 MODE
- MOV AL,'S' ; OF CITOH
- CALL SEND2
- MOV AL,'0'
- CALL SEND2
- MOV AL,'4'
- CALL SEND2
- MOV AL,'0'
- CALL SEND2
- MOV AL,'0'
- CALL SEND2
- ENDIF
- IF OTHER
- BP2
- ENDIF
- POP CX
- RET
- INDENT2 ENDP
- TST4 PROC NEAR ; This routine builds ONE bit plot byte
- MOV AX,80 ; by testing a dot with the mask sent
- SUB AX,CX ; from MLOOP.
- MOV SI,AX ; First it does the ODD row then the EVEN
- MOV AH,0 ; since alternate lines are offset 2000h
- MOV AL,[SI] ; from each other in memory.
- AND AL,DL ; DL has the mask
- CMP AL,0 ; SI the location
- JZ NO7 ; AL the memory byte
- CALL SET7 ; AH is the byte being built
- NO7: ADD SI,80 ; +80 gets us from say 0,0 to 2,0
- MOV AL,[SI] ; get the memory byte ( 4 dots )
- AND AL,DL ; get rid of dots we aren't testing now
- CMP AL,0 ; see if its COLOR 0
- JZ NO5 ; if yes, go on
- CALL SET5 ; otherwise set that bit
- NO5: ADD SI,80 ; continue 7 5 3 1
- MOV AL,[SI]
- AND AL,DL
- CMP AL,0
- JZ NO3
- CALL SET3
- NO3: ADD SI,80
- MOV AL,[SI]
- AND AL,DL
- CMP AL,0
- JZ NO1
- CALL SET1
- NO1: PUSH AX
- MOV AX,80
- SUB AX,CX ; CX counts our screen position
- ADD AX,2000H ; add 2000h for the EVEN rows
- MOV SI,AX ; with seg set to B800h we can use SI like an
- POP AX ; array pointer ( AH has our byte so don't lose )
- MOV AL,[SI] ; and continue with the same idea for 6 4 2 0
- AND AL,DL
- CMP AL,0
- JZ NO6
- CALL SET6
- NO6: ADD SI,80
- MOV AL,[SI]
- AND AL,DL
- CMP AL,0
- JZ NO4
- CALL SET4
- NO4: ADD SI,80
- MOV AL,[SI]
- AND AL,DL
- CMP AL,0
- JZ NO2
- CALL SET2
- NO2: ADD SI,80
- MOV AL,[SI]
- AND AL,DL
- CMP AL,0
- JZ NO0
- CALL SET0
- NO0: RET
- ; where's my Z80 now
- ; reverse this table if your bit plots use bit 0 for the top wire
- IF BIT7
- SET7: OR AH,80H ; top wire - bit 7
- RET
- SET6: OR AH,40H ; bit 6
- RET
- SET5: OR AH,20H ; bit 5
- RET
- SET4: OR AH,10H ; bit 4
- RET
- SET3: OR AH,08H ; bit 3
- RET
- SET2: OR AH,04H ; bit 2
- RET
- SET1: OR AH,02H ; bit 1
- RET
- SET0: OR AH,01H ; bit 0
- RET
- ENDIF
- IF BIT0
- SET7: OR AH,01H ; top wire - bit 0
- RET
- SET6: OR AH,02H ; bit 1
- RET
- SET5: OR AH,04H ; bit 2
- RET
- SET4: OR AH,08H ; bit 3
- RET
- SET3: OR AH,10H ; bit 4
- RET
- SET2: OR AH,20H ; bit 5
- RET
- SET1: OR AH,40H ; bit 6
- RET
- SET0: OR AH,80H ; bit 7
- RET
- ENDIF
- TST4 ENDP
- ; This routine pre-scans a line to see if in fact there are any bit
- ; plots to send. The main routine will keep sending bytes here
- ; If a whole line of 0's are sent we avoid going through the
- ; set-up for bit-plot (i.e. slower movement) graphics when a CR/LF
- ; would take care of everything.
- ; If there IS something to send, PTFLAG is set, the current line
- ; position is set to 0, bit-plot is init., and bits are really sent to printer.
- SEND PROC NEAR
- PUSH AX ; save the character
- PUSH DS ; DS saved cause it points to lines
- MOV AX,CS ; set seg for here
- MOV DS,AX ; This was some of my first stuff with the 8088
- POP AX ; and I see some needless complexity here now
- MOV CS:DSTOR,AX ; but it works and if I mess with it
- CMP CS:PTFLAG,0FFH ; its back to DEBUG.
- JNZ NOSEND ; if PTFLAG isn't FFh we are still scanning
- POP AX ; else get the char. in AL and print it
- CALL SEND2 ; this is the real out to printer routine
- JMP SHORT NOSET ; restore DS and return
- NOSEND: POP AX ; This is the SCAN routine
- CMP AL,0 ; get the char. > test for 0 > if so reset and go back
- JZ NOSET
- MOV AL,0FFH ; if <> 0
- MOV CS:PTFLAG,AL ; set PTFLAG to go
- POP AX ;DISCARD RETURN
- CMP CS:ONEOR2,1 ; check which (small or LARGE)
- JNZ TWO ; indent 6 or 13 depending on which routine
- CALL INDENT ; indent also sets up bit-plot mode
- CALL NOSET ; NOSET will restore DS to right pos.
- JMP MAIN ; and do the line for real.
- TWO: CALL INDENT2 ; init. for LARGE
- MOV SI,CS:WHERESI ; SI set back to start of line
- CALL NOSET ; get right DS
- JMP MAIN2A ; back to beginning
- NOSET: PUSH AX ; routine to restore DS
- MOV AX,CS:DSTOR
- MOV DS,AX
- POP AX
- RET
- SEND ENDP
- LFCR PROC NEAR ; send a regular CR/LF combo
- MOV AL,13
- CALL SEND2
- MOV AL,10
- CALL SEND2
- MOV AX,0
- MOV CS:PTFLAG,AL ; reset PTFLAG for next line
- MOV AX,CS:DSTOR ; restore DS
- MOV DS,AX
- RET ; onward
- LFCR ENDP
- BREAK? PROC NEAR ; Test for early exit
- PUSH AX ; don't lose any regs. here
- PUSH DX
- MOV AH,06H ; call direct keyboard io (constat)
- MOV DL,0FFH ; if we got a char. go check it.
- INT 21H
- JNZ GOBACK? ; if zero flag clear we have a character
- BCONT: POP DX ; no char. return
- POP AX
- RET
- GOBACK?:
- CMP AL,1BH ; ESC
- JZ BACK ; so go back, else return
- JMP SHORT BCONT ; no ESC exit
- BACK: POP DX ; ESC exit This doesn't check for Ctrl-Break
- POP AX ; so if it is hit we save it for the caller to handle
- POP AX ;DISCARD RETURN
- JMP DONE ; and go back to orig. caller
- BREAK? ENDP
- FLIPFLOP PROC NEAR ; This creates different combinations
- PUSH CX ; of a box of four bit-plot dots for one color dot.
- PUSH BX ; Don't lose any variables or loop counters
- PUSH AX
- MOV CL,2 ; AL has present bit-plot finished byte
- MOV BX,0
- AND AL,3 ; 00000011b
- CALL FLIP
- ROR BL,CL ; 11000000b
- POP AX ; basically rotate bits around for
- PUSH AX ; o x
- CALL R2 ; x o color 1
- AND AL,3 ; and
- CALL FLIP ; o x
- ROR BL,CL ; o x color 2
- POP AX ; instead of
- PUSH AX ; x o
- CALL R4 ; x o color 1
- AND AL,3 ; and
- CALL FLIP ; o x
- ROR BL,CL ; o x color 2
- POP AX ; which aren't to convincing as
- CALL R6 ; two different colors
- AND AL,3
- CALL FLIP
- ROR BL,CL
- MOV AL,BL
- POP BX
- POP CX
- RET
- R6: ROR AL,CL
- R4: ROR AL,CL
- R2: ROR AL,CL
- RET
- FLIP: CMP AL,3 ; make sure there are two dots for color 1 and 2
- JNZ FLIP2
- OR BL,3
- FLIP2: CMP AL,2
- JNZ FLIP3
- OR BL,1
- FLIP3: CMP AL,1
- JNZ FLIP4
- OR BL,1
- FLIP4: RET
- FLIPFLOP ENDP
- REVERSE PROC NEAR ; take AL and make bit 0 bit 7 , 1 - 6, etc
- PUSH DX ; Save our counters and masks
- PUSH CX
- MOV DL,01H ; 00000001B
- MOV DH,80H ; 10000000B
- MOV AH,00H ; start out blank
- MOV CX,8 ; set counter for 8 times through
- REV1: TEST AL,DL ; see if bit is set
- JZ REV2 ; if not skip next step
- OR AH,DH ; else set bit in AH
- REV2: SHL DL,1 ; shift left test bit
- SHR DH,1 ; shift right mask bit (pad other bits with 0)
- LOOP REV1 ; do this 8 times
- MOV AL,AH ; and we have a reversed character.
- POP CX ; get back these
- POP DX
- RET ; and back to caller
- REVERSE ENDP
- LAST DW 0
- CSEG ENDS
- END INIT
- sed